home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / MORPH.PL < prev    next >
Text File  |  1991-10-31  |  2KB  |  82 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5. /* Modified for Quintus Prolog by Andreas Siebert */
  6.  
  7. /* MORPH.PL */
  8.  
  9. /* Queries will use built-in predicate phrase/2 */
  10.  
  11. /* Parser for sentences with
  12.    verb-subject number agreement.
  13.    Like AGREEMNT.PL but includes
  14.    a few morphological rules. */
  15.  
  16. sentence --> noun_phrase(N), verb_phrase(N).
  17.  
  18. noun_phrase(N) --> determiner(N), noun(N).
  19.  
  20. verb_phrase(N) --> verb(N), noun_phrase(_).
  21. verb_phrase(N) --> verb(N), sentence.
  22.  
  23. determiner(singular) --> [a].
  24. determiner(_)        --> [the].
  25. determiner(plural)   --> [].
  26.  
  27. noun(N) --> [X], { morph(noun(N),X) }.
  28. verb(N) --> [X], { morph(verb(N),X) }.
  29.  
  30. /*
  31.  * morph(Type,Word)
  32.  *  succeeds if Word is a word-form
  33.  *  of the specified type.
  34.  */
  35.  
  36. /* Singular (unmarked) nouns */
  37.  
  38. morph(noun(singular),dog).
  39. morph(noun(singular),cat).
  40. morph(noun(singular),boy).
  41. morph(noun(singular),girl).
  42. morph(noun(singular),child).
  43.  
  44. /* Irregular plural nouns */
  45.  
  46. morph(noun(plural),children).
  47.  
  48. /* Rule for regular plural nouns */
  49.  
  50. morph(noun(plural),X) :-
  51.      remove_s(X,Y),
  52.      morph(noun(singular),Y).
  53.  
  54. /* Plural (unmarked) verbs */
  55.  
  56. morph(verb(plural),chase).
  57. morph(verb(plural),see).
  58. morph(verb(plural),say).
  59. morph(verb(plural),believe).
  60.  
  61. /* Rule for singular verbs */
  62.  
  63. morph(verb(singular),X) :-
  64.      remove_s(X,Y),
  65.      morph(verb(plural),Y).
  66.  
  67. /*
  68.  * remove_s(X,X1) [lifted from TEMPLATE.PRO]
  69.  *  removes final S from X giving X1,
  70.  *  or fails if X does not end in S.
  71.  */
  72.  
  73. remove_s(X,X1) :-
  74.      name(X,XList),
  75.      remove_s_list(XList,X1List),
  76.      name(X1,X1List).
  77.  
  78. remove_s_list("s",[]).
  79.  
  80. remove_s_list([Head|Tail],[Head|NewTail]) :-
  81.      remove_s_list(Tail,NewTail).
  82.